TableGetFromUnit Subroutine

private subroutine TableGetFromUnit(unit, tab, id)

read a table from specified file unit. File is already open. Arguments: unit file in which table is contained tab returned table id optional, id of table to read

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: unit
type(Table), intent(out) :: tab
character(len=*), intent(in), optional :: id

Variables

Type Visibility Attributes Name Initial
integer(kind=long), public :: count
integer(kind=short), public :: ios
integer(kind=long), public :: j
character(len=LINELENGTH), public, POINTER :: lines(:)
character(len=300), public :: string

Source Code

SUBROUTINE TableGetFromUnit &
  ( unit, tab, id )

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
INTEGER (KIND = short), INTENT(IN) :: unit
CHARACTER (LEN = *), OPTIONAL, INTENT (IN) :: id

! Array arguments with intent (out):
TYPE (Table), INTENT (OUT) :: tab

! Local scalars:
INTEGER (KIND = short) :: ios
INTEGER (KIND = long)  :: count
INTEGER (KIND = long)  :: j
CHARACTER (LEN = 300)  :: string

! Local Arrays:
CHARACTER (LEN = LINELENGTH), POINTER :: lines (:)

!------------end of declaration------------------------------------------------

!search beginning of table
IF (PRESENT(id)) THEN
  ios = TableFileSync (unit, id = id)
ELSE
  ios = TableFileSync (unit)
END IF

!Store significant lines in memory
CALL TableStoreLines ( unit, lines )
!Get title
tab % title = TableReadTitle (lines)
!get Id
tab % id = TableReadId (lines)
!count number of columns
tab % noCols = TableCountCols (lines)
IF ( tab % noCols == 0) THEN
  CALL Catch ('error', 'TableLib', 'no columns found in table: ', &
               argument = tab % id)
END IF
!allocate columns
ALLOCATE ( tab % col ( tab % noCols ) )
!count number of rows
tab % noRows = TableCountRows (lines)
!allocate rows
DO j = 1, tab % noCols
  ALLOCATE ( tab % col (j) % row ( tab % noRows ) )
END DO
!read header unit and content of the tables.
CALL TableReadHeader ( lines, tab )

CALL TableReadUnit ( lines, tab )

CALL TableReadContent ( lines, tab )

!table is initialized: deallocate lines
DEALLOCATE (lines)

END SUBROUTINE TableGetFromUnit